home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
prolog
/
brklyprl.lha
/
Comp
/
varlist.pl
< prev
next >
Wrap
Text File
|
1989-04-14
|
3KB
|
81 lines
/* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
/* Copyright Herve' Touati, Aquarius Project, UC Berkeley */
% Calculate from the unraveled source code
% the varlist used for calculating lifetimes.
% All goal arguments (variables & atoms) are simply listed.
% For unify goals only the variables are listed.
% Goal arguments are delimited by one or both of arity(Arity) and fence(Name).
% This is determined as follows:
% 1. arity(Arity) allows tempalloc to do more optimal allocation.
% It comes before the arguments.
% It is generated for all goals, even built-ins (except unify,
% or goals with arity zero).
% 2. fence(Name) is used in lifetime to kill temporaries.
% It comes after the arguments.
% It is not generated for built-ins or the head of the clause.
%
% 11/15/84:
% Correction - last line of item 1 used to be:
%
% or goals with arity zero, or if all arguments are nonvariable).
%
% This is incorrect because even nonvariable arguments will use registers,
% so tempalloc will have to be made aware of them.
% Fourth line of goalsvars used to be
% ((Arity=0;getvars(Args, []-[])) -> Vars=L;
varlist([Head|RestCode], [arity(Arity)|Vars]) :-
Head=..[Name|Args],
my_length(Args, Arity),
linkify(Args, Vars-L),
xvarlist(RestCode, L-[]), !.
xvarlist([X|RestCode], [Dis|Vars]-Link) :-
X=(_;_),
dislist(X, Dis),
xvarlist(RestCode, Vars-Link).
xvarlist([Goal|RestCode], Vars-Link) :-
goalsvars(Goal, Vars-L),
xvarlist(RestCode, L-Link).
xvarlist([], Link-Link).
dislist((A;B), (AVars;BVars)) :-
xvarlist(A, AVars-[]),
dislist(B, BVars).
dislist(B, BVars) :-
xvarlist(B, BVars-[]).
goalsvars(A=S, Vars_Link) :-
var(S), !,
getvars([A,S], Vars_Link).
goalsvars(A=S, Vars_Link) :-
list(S), !,
getvars([A|S], Vars_Link).
goalsvars(A=S, Vars_Link) :-
atom(S), !,
getvars([A], Vars_Link).
goalsvars(A=S, Vars_Link) :-
S=..[_|SVars],
getvars([A|SVars], Vars_Link).
goalsvars(Goal, Link-Link) :-
atom(Goal), escape_builtin(Goal,0), !.
goalsvars(Goal, [fence(Name)|Link]-Link) :-
atom(Goal), !.
% Added clause for VLSI PLM:
% goalsvars(is(Out,A,Op,B), [arity(1)|Vars]-Link) :-
% compile_options(s),
% vlsi_instr(Op,_), !,
% getvars([A,B,Out], Vars-Link).
goalsvars(Goal, [arity(Arity)|V]-Link) :-
Goal=..[Name|Args],
my_length(Args,Arity),
escape_builtin(Name,Arity), !,
linkify(Args, V-Link).
goalsvars(Goal, [arity(Arity)|V]-Link) :-
Goal=..[Name|Args],
my_length(Args,Arity),
linkify(Args, V-[fence(Name)|Link]).